home *** CD-ROM | disk | FTP | other *** search
- PAGE 59, 132
-
- TITLE MSXRB -- Machine dependent module for DEC Rainbow
-
- ; Update 23 Nov 85
-
- IF1
- %OUT >> Starting pass 1
- ELSE
- %OUT >> Starting pass 2
- ENDIF
-
- ; Kermit system dependent module for Rainbow
- ; Jeff Damens, July 1984
-
- public SerIni_RB, SerRst_RB, ClrBuf_RB, OutChr_RB, Coms_RB
- public VTS_RB, DoDel_RB, CtlU_RB, CmBlnk_RB, Locate_RB
- public LclIni_RB, PrtChr_RB, DoBaud_RB, ClearL_RB, Drop_DTR_RB
- public DoDisk_RB, GetBaud_RB, Beep_RB, Close_screen_RB
- public PutHlp_RB, PutMod_RB, ClrMod_RB, PosCur_RB
- public SendBR_RB, Term_RB, SetKTab_RB, SetKHlp_RB, ShowKey_RB
- PUBLIC Set_up_script_processor_RB
- include msdefs.h
-
- ; rainbow-dependent screen constants
-
- scrseg equ 0ee00H ; screen segment
- latofs equ 0ef4h ; ptrs to line beginnings, used by firmware
- csrlin equ 0f42h ; current cursor line.
-
- ; level 1 console definitions
-
- fnkey equ 100H ; function key flag
- shfkey equ 200H ; shift key
- ctlkey equ 400H ; control key
- cplk equ 800H
-
- brkkey equ 65H
- prtkey equ 3
- Cntrl_E EQU 5
-
- false equ 0
- true equ 1
- mntrgh equ bufsiz*3/4 ; High point = 3/4 of buffer full.
-
- mnstata equ 042H ;Status/command port A
- mnstatb equ 043H ;Status/command port B.
- mndata equ 040H ;Data port.
- mndatb equ 041H
- mnctrl equ 002H ;Control port.
- serchn equ 0A4H ; interrupt to use
- serch1 equ 044H ; use this too for older rainbows.
-
- txrdy EQU 04H ;Bit for output ready.
- rxrdy EQU 01H ;Bit for input ready.
-
- fastcon equ 29H ; fast console handler
- firmwr equ 18H
-
- swidth equ 132 ; screen width
- slen equ 24 ; screen length
-
- stbrk equ 15 ; start sending a break
- enbrk equ 16 ; stop sending break.
-
- ; external variables used:
- ; drives - # of disk drives on system
- ; flags - global flags as per flginfo structure defined in pcdefs
- ; trans - global transmission parameters, trinfo struct defined in pcdefs
- ; portval - pointer to current portinfo structure (currently either port1
- ; or port2)
- ; port1, port2 - portinfo structures for the corresponding ports
-
- ; global variables defined in this module:
- ; xofsnt, xofrcv - tell whether we saw or sent an xoff.
-
- ; circular buffer ptr
- cbuf struc
- pp dw ? ; place ptr in buffer
- bend dw ? ; end of buffer
- orig dw ? ; buffer origin
- lcnt dw 0 ; # of lines in buffer.
- cbuf ends
-
- ; answerback structure
- ans struc
- anspt dw ? ; current pointer in answerback
- ansct db ? ; count of chars in answerback
- ansseq dw ? ; pointer to whole answerback
- anslen db ? ; original length
- ansrtn dw ? ; routine to call.
- ans ends
-
- datas segment public 'datas'
- extrn drives:byte,flags:byte, trans:byte, Source:BYTE
- extrn portval:word, port1:byte, port2:byte, SrcPnt:WORD
- EXTRN Count:WORD, XofSnt:BYTE
-
- Escape_key_mode_line db ' ? = Help C = Close S = Status B = Send Break ? For Full List$'
-
- Terminal_message db '( Entering terminal mode:',cr,lf,' Press <Do> or Ctrl-] C to return to Local BTLink )',cr,lf,'$'
-
- SetKTab_RB DB 22
- mkeyw 'F4',fnkey+5h
- mkeyw 'F5',fnkey+65h
- mkeyw 'F6',fnkey+7h
- mkeyw 'F7',fnkey+9h
- mkeyw 'F8',fnkey+0Bh
- mkeyw 'F9',fnkey+0Dh
- mkeyw 'F10',fnkey+0Fh
- mkeyw 'F11',esc
- mkeyw 'F12',bs
- mkeyw 'F13',lf
- mkeyw 'F14',fnkey+11h
- mkeyw 'F17',fnkey+13h
- mkeyw 'F18',fnkey+15h
- mkeyw 'F19',fnkey+17h
- mkeyw 'F20',fnkey+19h
- mkeyw 'FIND',fnkey+1bh
- mkeyw 'INSERTHERE',fnkey+1dh
- mkeyw 'REMOVE',fnkey+1fh
- mkeyw 'SCAN',-1
- mkeyw 'SELECT',fnkey+21h
-
- Seventy_nine_blanks_then_cr DB 79 DUP(' '), Cr, '$'
-
- ourflgs db Which_mode ; our flags
- ; flag definitions...
- fpscr equ 80H ; Flag for Ctrl-Print-Screen functionality
- MC_Pcon equ 40H ; Flag for Printer Controller (MC)
- ; escape sequence processing
- Which_mode EQU 20H ; Flag that we are really at "BTLink> " screen
- ; instead of terminal emulation screen
-
- crlf db cr,lf
- SetKHlp_RB DB ' F4 ... F20 or SCAN$'
- nyimsg db cr,lf,'Not yet implemented$'
- delstr db BS,' ',BS,'$' ; Delete string.
- clrlin db cr,'$' ; Clear line (just the cr part).
- oldser dw ? ; old serial handler
- oldseg dw ? ; segment of above
- old1ser dw ? ; old serial handler, alternate address
- old1seg dw ? ; segment of same.
- portin db 0 ; Has comm port been initialized.
- xofrcv db 0 ; Say if we received an XOFF.
- iobuf db 5 dup (?) ; buffer for ioctl
-
- phbuf db swidth dup (?)
- gopos db esc,'['
- rowp db 20 dup (?)
- clrseq db esc,'[H',esc,'[J$'
- ceolseq db esc,'[K$'
- invseq db esc,'[7m$'
- nrmseq db esc,'[0m$'
- ivlatt db swidth dup (0fH) ; a line's worth of inverse attribute
-
- ; special keys.
- spckey dw brkkey,prtkey,prtkey+ctlkey
- spclen equ ($-spckey)/2
- ; special key handlers. Must parallel spckey
- spchnd dw SendBR_RB,prtscr,togprt
-
- ; arrow and PF keys
- arrkey db 27H,29H,2bH,2dH,59H,5cH,5fH,62H
- arrlen equ $-arrkey
- ; translations for arrow and PF keys, must parallel arrkey
- arrtrn dw uptrn,dntrn,rgttrn,lfttrn
- dw pf1trn,pf2trn,pf3trn,pf4trn
-
- ; keypad keys
- keypad db 2fh,32h,35h,38h,3bh,3eh,41h,44h,47h,4ah,4dh,50h,53h,56h
- keypln equ $-keypad
- ; keytrn and altktrn must parallel keypad
- keytrn db '0123456789-,.',cr
- altktrn db 'pqrstuvwxymlnM'
-
- keyptr dw keytrn ; pointer to correct translation table
- akeyflg db 0 ; non-zero if in alt keypad mode.
-
- ; arrow and PF key translations
- uptrn db 3,esc,'[A'
- dntrn db 3,esc,'[B'
- rgttrn db 3,esc,'[C'
- lfttrn db 3,esc,'[D'
- pf1trn db 3,esc,'OP'
- pf2trn db 3,esc,'OQ'
- pf3trn db 3,esc,'OR'
- pf4trn db 3,esc,'OS'
-
- ourarg termarg <>
-
- EVEN
-
- Script_processor DW 0 ; Address of script processor to run
-
- ; variables for serial interrupt handler
- savesi dw 0 ; Save SI register here.
-
- telflg db 0 ; non-zero if we're a terminal. NRU.
- respkt db 10 dup (?) ; ioctl packet
-
- ivec dw tranb ; transmit empty B
- dw tranb ; status change B
- dw tranb ; receive b
- dw tranb ; special receive b
- dw stxa ; transmit empty a
- dw sstata ; status change a
- dw srcva ; receive a
- dw srcva ; special receive a
-
- ; screen stuff
-
- prbuf db swidth dup (?) ; print temp buffer
- topdwn db esc,'[H',esc,'M$' ; go to top, scroll down
- botup db esc,'[24;0H',esc,'D$' ; go to bottom, scroll up
- curinq db esc,'[6n$' ; cursor inquiry
- posbuf db 12 dup (?) ; place to store cursor position
- command_posbuf db 12 dup (?) ; place to store BTLink
- ; command screen cursor position
- gtobot db esc,'[24;0H$' ; go to bottom of screen.
- ourscr db slen*swidth dup (?)
- ourattr db slen*swidth dup (?) ; storage for screen and attributes
- command_mode_screen db slen*swidth dup (?) ; buffer for screen
- command_mode_attrs db slen*swidth dup (?) ; buffer for attribute
- inited db 0 ; terminal handler not inited yet.
- dosmsg db '?Must be run in version 2.05 or higher$'
- anssq1 db esc,'[5i' ; Turn Printer Controller on
- ansln1 equ $-anssq1
- anssq2 db esc,'[4i' ; Turn Printer Controller off
- ansln2 equ $-anssq2
- eakseq db esc,'='
- dakseq db esc,'>'
- Do_Server_mode_Sq DB ESC,'[17J'
- Req_to_ident_seq DB ESC,'[18J'
- Identification_sequence DB ESC,'[?99c'
- Length_of_identification_sequence EQU $-Identification_sequence
- ansbk1 ans <anssq1,ansln1,anssq1,ansln1,Printer_Controller_MC>
- ansbk2 ans <anssq2,ansln2,anssq2,ansln2,Printer_Controller_MC>
- ansbk3 ans <eakseq,2,eakseq,2,enaaky> ; enable alt keypad
- ansbk4 ans <dakseq,2,dakseq,2,deaaky> ; disable alt keypad
- ansbk5 ans <Do_Server_mode_Sq,5,Do_Server_mode_Sq,5,Do_Server_mode>
- ansbk6 ans <Req_to_ident_seq,5,Req_to_ident_seq,5,Identify>
- Partial_esc_seq DB ESC,'[17$' ; For TSMG typing in Do_Server_mode
-
- shkbuf db 300 dup (?) ; room for definition
- shkmsg db ' Scan code: '
- shkmln equ $-shkmsg
- shkms1 db cr,lf,' Definition: '
- shkm1ln equ $-shkms1
- datas ends
-
- code segment public
- extrn Quit_emulator:BYTE, comnd:near, dopar:near, Enter_Server:NEAR
- assume cs:code,ds:datas
-
- ; local initialization routine, called by Kermit initialization.
-
- LclIni_RB proc near
- ; make sure this is DOS version 2.05 or higher...
- mov ah,dosver
- int dos
- xchg al,ah ; put major version in ah, minor in al
- cmp ax,205H ; is it 2.05?
- jae lclin1 ; yes, go on
- mov dx,offset dosmsg
- call tmsg
- mov ax,4c00H ; exit(0)
- int dos
- lclin1: mov flags.vtflg,0 ; turn off heath emulation
- ret
- LclIni_RB endp
-
- ; this is called by Kermit initialization. It checks the
- ; number of disks on the system, sets the drives variable
- ; appropriately. The only problem is that a value of two
- ; is returned for single drive systems to be consistent
- ; with the idea of the system having logical drives A and
- ; B. Returns normally.
-
- DoDisk_RB PROC NEAR
- mov ah,gcurdsk ; Current disk value to AL.
- int dos
- mov dl,al ; Put current disk in DL.
- mov ah,seldsk ; Select current disk.
- int dos ; Get number of drives in AL.
- mov drives,al
- ret
- DoDisk_RB ENDP
-
- ; show the definition of a key. The terminal argument block (which contains
- ; the address and length of the definition tables) is passed in ax.
- ; Returns a string to print in AX, length of same in CX.
- ; Returns normally.
- ShowKey_RB proc near
- push es
- push ax ; save the ptr
- cld
- showk1: mov di,6 ; get level one char
- int firmwr
- cmp cl,0ffH
- jne showk1 ; wait until char available
- mov bx,ds
- mov es,bx ; address data segment
- and ax,not cplk ; no caps lock
- push ax ; remember scan code
- mov di,offset shkbuf
- mov si,offset shkmsg
- mov cx,shkmln
- rep movsb ; copy in initial message
- call nout ; write out scan code
- mov si,offset shkms1
- mov cx,shkm1ln ; second message
- rep movsb
- pop ax ; get scan code back
- pop bx ; and terminal arg block
- mov cx,[bx].klen ; and length
- jcxz showk2 ; no table, not defined
- push di ; remember output ptr
- mov di,[bx].ktab ; get key table
- repne scasw ; search for a definition for this
- mov si,di ; remember result ptr
- pop di ; get output ptr back
- jne showk2 ; not defined, forget it
- sub si,[bx].ktab ; compute offset from beginning
- sub si,2 ; minus 2 for pre-increment
- add si,[bx].krpl ; get index into replacement table
- mov si,[si] ; pick up replacement
- mov cl,[si] ; get length
- mov ch,0
- inc si
- rep movsb ; copy into buffer
- showk2: mov ax,offset shkbuf ; this is buffer
- mov cx,di
- sub cx,ax ; length
- pop es
- ret ; and return
- ShowKey_RB endp
-
- ; Clear the input buffer. This throws away all the characters in the
- ; serial interrupt buffer. This is particularly important when
- ; talking to servers, since NAKs can accumulate in the buffer.
- ; Returns normally.
-
- ClrBuf_RB PROC NEAR
- cli
- mov ax,offset Source
- mov srcpnt,ax
- mov savesi,ax
- mov count,0
- sti
- ret
- ClrBuf_RB ENDP
-
- ; Clear to the end of the current line. Returns normally.
-
- ClearL_RB PROC NEAR
- mov dx,offset ceolseq ; clear sequence
- jmp tmsg
- ClearL_RB ENDP
-
- ; Put the char in AH to the serial port. This assumes the
- ; port has been initialized. Should honor xon/xoff. Skip returns on
- ; success, returns normally if the character cannot be written.
-
- OutChr_RB:
- mov bp,portval
- cmp ds:[bp].floflg,0 ; Are we doing flow control.
- je outch2 ; No, just continue.
- xor cx,cx ; clear counter
- outch1: cmp xofrcv,true ; Are we being held?
- jne outch2 ; No - it's OK to go on.
- loop outch1 ; held, try for a while
- mov xofrcv,false ; timed out, force it off and fall thru.
- outch2: push dx ; Save register.
- sub cx,cx
- mov al,ah ; Parity routine works on AL.
- call dopar ; Set parity appropriately.
- mov ah,al ; Don't overwrite character with status.
- mov dx,mnstata ; port status register
- outch3: in al,dx
- test al,txrdy ; Transmitter ready?
- jnz outch4 ; Yes
- loop outch3
- jmp outch5 ; Timeout
- outch4: mov al,ah ; Now send it out
- mov dx,mndata
- out dx,al
- pop dx
- jmp rskp
- outch5: pop dx
- ret
-
- ; This routine blanks the screen. Returns normally.
-
- CmBlnk_RB PROC NEAR
- mov dx,offset clrseq ; clear screen sequence
- jmp tmsg
- CmBlnk_RB ENDP
-
- ; Locate_RB; homes the cursor. Returns normally.
-
- Locate_RB PROC NEAR
- mov dx,0 ; Go to top left corner of screen.
- jmp PosCur_RB
- Locate_RB ENDP
-
- ; write a line in inverse video at the bottom of the screen...
- ; the line is passed in dx, terminated by a $. Returns normally.
-
- PutMod_RB proc near
-
- push dx ; preserve message
- mov dx,24 * 100H ; line 24
- call PosCur_RB
- mov dx,offset invseq ; put into inverse video
- call tmsg
- mov dx, OFFSET Seventy_nine_blanks_then_cr ; Blank the line
- call tmsg
- pop dx
- call tmsg ; print the message
- mov dx,offset nrmseq ; normal video
- jmp tmsg
-
- PutMod_RB endp
-
- ; clear the mode line written by PutMod_RB. Returns normally.
- ClrMod_RB proc near
- mov dx,24 * 100H
- call PosCur_RB
- call ClearL_RB
- ret
- ClrMod_RB endp
-
- ; Put a help message on the screen. This one uses reverse video...
- ; pass the message in ax, terminated by a null. Returns normally.
- PutHlp_RB proc near
- push ax
- mov dx,slen * 100H ; go to bottom line
- call PosCur_RB
- pop ax
- push es
- mov bx,ds
- mov es,bx ; address data segment
- mov si,ax ; convenient place for this
- mov bx,101H ; current line/position
- puthl1: mov di,offset phbuf ; this is destination
- xor cx,cx ; # of chars in the line
- puthl2: lodsb ; get a byte
- cmp al,cr ; carriage return?
- je puthl2 ; yes, ignore it
- cmp al,lf ; linefeed?
- je puthl3 ; yes, break the loop
- cmp al,0
- je puthl3 ; ditto for null
- dec cx ; else count the character
- stosb ; deposit into the buffer
- jmp puthl2 ; and keep going
- puthl3: add cx,80 ; this is desired length of the whole
- mov al,' '
- rep stosb ; fill the line
- push bx
- push si
- push es ; firmware likes to eat this one
- mov ax,0 ; send chars and attributes
- mov cx,80 ; this is # of chars to send
- mov dx,offset ivlatt ; this are attributes to send
- mov si,offset phbuf ; the actual message
- mov di,14H ; send direct to screen
- mov bp,ds ; need data segment as well
- int firmwr ; go send it
- pop es
- pop si
- pop bx ; restore everything
- inc bx ; next line
- cmp byte ptr [si-1],0 ; were we ended by a 0 last time?
- jne puthl1 ; no, keep looping
- pop es ; else restore this
- ret ; and return
- PutHlp_RB endp
-
- ; Set the baud rate for the current port, based on the value
- ; in the portinfo structure. Returns normally.
-
- ; no baud rate.
- DoBaud_RB PROC NEAR
- mov dx,offset nyimsg
- call tmsg
- mov bx,portval
- mov [bx].baud,-1 ; keep baud rate unknown.
- ret
- DoBaud_RB ENDP
-
- ; Get the current baud rate from the serial card and set it
- ; in the portinfo structure for the current port. Returns normally.
- ; This is used during initialization.
-
- GetBaud_RB PROC NEAR
- ret ; no baud rate for now.
- GetBaud_RB ENDP
-
-
- ; skip returns if no character available at port,
- ; otherwise returns with char in al, # of chars in buffer in dx.
- PrtChr_RB PROC NEAR
- call chkxon ; see if we have to xon the host.
- cmp count,0
- jnz prtch2
- jmp rskp ; No data - check console.
- prtch2: mov si,savesi
- lodsb ; get a byte
- cmp si,offset Source + bufsiz ; bigger than buffer?
- jb prtch1 ; no, keep going
- mov si,offset Source ; yes, wrap around
- prtch1: dec count
- mov savesi,si
- mov dx,count ; return # of chars in buffer
- ret
- PrtChr_RB ENDP
-
- ; local routine to see if we have to transmit an xon
- chkxon proc near
- push bx
- mov bx,portval
- cmp [bx].floflg,0 ; doing flow control?
- je chkxo1 ; no, skip all this
- cmp xofsnt,false ; have we sent an xoff?
- je chkxo1 ; no, forget it
- cmp count,mntrgh ; below trigger?
- jae chkxo1 ; no, forget it
- mov ax,[bx].flowc ; ah gets xon
- call OutChr_RB ; send it
- nop
- nop
- nop ; in case it skips
- mov xofsnt,false ; remember we've sent an xon.
- chkxo1: pop bx ; restore register
- ret ; and return
- chkxon endp
-
- ; Send a break out the current serial port. Returns normally.
- SendBR_RB PROC NEAR
- push bx
- push cx
- push dx
- push ax
- mov ah,ioctl
- mov al,3 ; write to control channel.
- mov bx,3 ; aux port handle
- mov dx,offset iobuf
- mov iobuf,stbrk ; start sending a break
- int dos
- xor cx,cx ; clear loop counter
- pause: loop pause ; Wait a while.
- mov ah,ioctl
- mov al,3
- mov bx,3
- mov dx,offset iobuf
- mov iobuf,enbrk ; stop sending the break
- int dos
- pop ax
- pop dx
- pop cx
- pop bx
- ret ; And return.
- SendBR_RB ENDP
-
- ; Position the cursor according to contents of DX:
- ; DH contains row, DL contains column. Returns normally.
-
- PosCur_RB PROC NEAR
- add dx,101H ; start at 1,1
- push es
- push dx
- cld
- mov ax,ds
- mov es,ax ; address right segment
- mov di,offset rowp
- mov al,dh ; row comes first
- mov ah,0
- call nout
- mov al,';'
- stosb ; separated by a semi
- pop dx
- mov al,dl
- mov ah,0
- call nout
- mov al,'H'
- stosb ; end w/H
- mov byte ptr [di],'$' ; and dollar sign
- mov dx,offset gopos
- call tmsg
- pop es
- ret
- PosCur_RB ENDP
-
- ; Delete a character from the terminal. This works by printing
- ; backspaces and spaces. Returns normally.
-
- DoDel_RB PROC NEAR
- mov dx,offset delstr ; Erase weird character.
- jmp tmsg
- DoDel_RB ENDP
-
- ; Move the cursor to the left margin, then clear to end of line.
- ; Returns normally.
-
- CtlU_RB PROC NEAR
- mov dx,offset clrlin ; this just goes to left margin...
- call tmsg
- jmp ClearL_RB ; now clear line
- CtlU_RB ENDP
-
- ; set the current port.
-
- Coms_RB PROC NEAR
- mov dx,offset nyimsg
- jmp tmsg
- Coms_RB ENDP
-
- ; Set heath emulation on/off.
-
- VTS_RB PROC NEAR
- mov dx,offset nyimsg
- jmp tmsg
- VTS_RB ENDP
-
- ; initialization for using serial port. This routine performs
- ; any initialization necessary for using the serial port, including
- ; setting up interrupt routines, setting buffer pointers, etc.
- ; Doing this twice in a row should be harmless (this version checks
- ; a flag and returns if initialization has already been done).
- ; SerRst_RB below should restore any interrupt vectors that this changes.
- ; Returns normally.
-
- SerIni_RB PROC NEAR
- push es
- cmp portin,0 ; Did we initialize port already? [21c]
- jne serin0 ; Yes, so just leave. [21c]
- cli ; Disable interrupts
- cld ; Do increments in string operations
- xor ax,ax ; Address low memory
- mov es,ax
- mov ax,es:[4*serchn] ; get old serial handler
- mov oldser,ax ; save.
- mov ax,es:[4*serchn+2] ; get segment
- mov oldseg,ax ; save segment as well
- mov ax,es:[4*serch1] ; this is alternate for older rainbows
- mov old1ser,ax
- mov ax,es:[4*serch1+2]
- mov old1seg,ax ; pretty silly, huh?
- mov ax,offset serint ; point to our routine
- mov word ptr es:[4*serchn],ax ; point at our serial routine
- mov word ptr es:[4*serch1],ax ; have to set both of these
- mov es:[4*serchn+2],cs ; our segment
- mov es:[4*serch1+2],cs
- mov al,0F0h ; [DTR] enable RTS and DTR
- out mnctrl,al ; [DTR]
- mov portin,1 ; Remember port has been initialized.
- call ClrBuf_RB ; Clear input buffer.
- sti ; Allow interrupts
- serin0: pop es
- ret ; We're done.
- SerIni_RB ENDP
-
- ; this is used to by SerIni_RB
- prtset proc near
- lodsb ; get a byte
- or al,al
- jz prtse1 ; end of table, stop here
- out dx,al ; else send it out
- jmp prtset ; and keep looping
- prtse1: ret ; end of routine
- prtset endp
-
- ; Reset the serial port. This is the opposite of SerIni_RB. Calling
- ; this twice without intervening calls to SerIni_RB should be harmless.
- ; Returns normally.
-
- SerRst_RB PROC NEAR
- push es ; preserve this
- cmp portin,0 ; Reset already?
- je srst1 ; Yes, just leave.
- cli ; Disable interrupts
- xor ax,ax
- mov es,ax ; address segment 0
- mov ax,oldser
- mov es:[4*serchn],ax
- mov ax,oldseg
- mov es:[4*serchn+2],ax
- mov ax,old1ser
- mov es:[4*serch1],ax
- mov ax,old1seg
- mov es:[4*serch1+2],ax ; restore old handlers
- mov portin,0 ; Reset flag.
- srst1: pop es
- ret ; All done.
- SerRst_RB ENDP
-
-
- Drop_DTR_RB PROC
-
- ; This is just a guess on how to do this ... but, the following two lines
- ; of code seem to be the ones which turn on RTS and DTR. Lets try using
- ; the opposite (?) to turn off those signals.
- ;
- ; mov al,0F0h ; [DTR] enable RTS and DTR
- ; out mnctrl,al ; [DTR]
-
- push ax ; Save reg
- sub al, al ; Make a zero
- out mnctrl, al ; Try to turn off DTR and RTS
- pop ax ; Restore reg
- ret ; Done here
-
- Drop_DTR_RB ENDP
-
-
- %OUT >> About half way through source file
-
- ; serial port interrupt routine. This is not accessible outside this
- ; module, handles serial port receiver interrupts.
-
- serint PROC NEAR
- push bx
- push dx
- push ax
- push es
- push di
- push ds
- push bp
- push cx
- cld
- mov ax,seg datas
- mov ds,ax ; address data segment
- mov es,ax
- mov di,srcpnt ; Registers for storing data.
- mov dx,mnstatb ; Asynch status port.
- mov al,0 ; innocuous value
- out dx,al ; send out to get into a known state...
- mov al,2 ; now address register 2
- out dx,al
- in al,dx ; read interrupt cause
- cmp al,7 ; in range?
- ja serin7 ; no, just dismiss (what about reset error?)
- mov bl,al
- shl bl,1 ; double for word index
- mov bh,0
- call ivec[bx] ; call appropriate handler
- serin7: mov dx,mnstata ; reload port address
- mov al,38H
- out dx,al ; tell the port we finished with the interrupt
- pop cx
- pop bp
- pop ds
- pop di
- pop es
- pop ax
- pop dx
- pop bx
- intret: iret
-
- ; handler for serial receive, port A
- srcva: mov dx,mnstata
- mov al,0
- out dx,al ; put into known state...
- in al,dx
- test al,rxrdy ; Data available?
- jnz srcva1 ; yes, go read it
- jmp srcva7
- srcva1: mov al,30H ; reset any errors
- out dx,al
- mov dx,mndata
- in al,dx ; read the character
- cmp telflg,0 ; File transfer or terminal mode?
- jz srcva2
- and al,7FH ; Terminal mode (7 bits only).
-
- srcva2: or al,al
- jz srcva7 ; Ignore nulls.
- cmp al,7FH ; Ignore rubouts, too.
- jz srcva7
- mov ah,al
- and ah,7fH ; only consider low-order 7 bits for flow ctl.
- mov bp,portval
- cmp ds:[bp].floflg,0 ; Doing flow control?
- je srcva4 ; Nope.
- mov bx,ds:[bp].flowc ; Flow control char (BH = XON, BL = XOFF).
- cmp ah,bl ; Is it an XOFF?
- jne srcva3 ; Nope, go on.
- mov xofrcv,true ; Set the flag.
- jmp short srcva7
- srcva3: cmp ah,bh ; Get an XON?
- jne srcva4 ; No, go on.
- mov xofrcv,false ; Clear our flag.
- jmp srcva7
- srcva4: stosb
- cmp di,offset Source + bufsiz
- jb srcva5 ; not past end...
- mov di,offset Source ; wrap buffer around
- srcva5: mov srcpnt,di ; update ptr
- inc count
- cmp ds:[bp].floflg,0 ; Doing flow control?
- je srcva7 ; No, just leave.
- cmp xofsnt,true ; Have we sent an XOFF?
- je srcva7 ; Yes.
- cmp count,mntrgh ; Past the high trigger point?
- jbe srcva7 ; No, we're within our limit.
- mov ah,bl ; Get the XOFF.
- call OutChr_RB ; Send it.
- nop
- nop
- nop ; ignore failure.
- mov xofsnt,true ; Remember we sent it.
- srcva7: ret
-
- ; The interrupt is for the 'B' port - transfer control to
- ; the original handler and hope for the best.
- tranb: pushf ; put flags on stack to simulate interrupt
- call dword ptr [old1ser] ; call old handler
- ret ; and return
-
- stxa: mov dx,mnstata
- mov al,28H ; reset transmit interrupt
- out dx,al
- ret
-
- sstata: mov dx,mnstata
- mov al,10H ; reset status interrupt
- out dx,al
- ret
-
- SERINT ENDP
-
- ; Produce a short beep. Returns normally.
-
- Beep_RB PROC NEAR
- mov dl,bell
- mov ah,conout
- int dos
- ret
- Beep_RB ENDP
-
- ; put the number in ax into the buffer pointed to by di. Di is updated
- nout proc near
- mov dx,0 ; high order is always 0.
- mov bx,10
- div bx ; divide to get digit
- push dx ; save remainder digit
- or ax,ax ; test quotient
- jz nout1 ; zero, no more of number
- call nout ; else call for rest of number
- nout1: pop ax ; get digit back
- add al,'0' ; make printable
- stosb ; drop it off
- ret ; and return
- nout endp
-
-
- Term_RB proc near
- mov si,ax ; this is source
- mov di,offset ourarg ; place to store arguments
- mov ax,ds
- mov es,ax ; address destination segment
- mov cx,size termarg
- cld
- rep movsb ; copy into our arg blk
- Test ourflgs, Which_mode ; Are we at terminal emulation screen
- jZ terma ; Yes - so don't save it as BTLink
- ; command screen
- call Save_command_mode_screen ; Save BTLink command screen
- terma: Cmp inited, 0 ; Inited yet?
- jNE term0 ; Yes - skip message
- Call CmBlnk_RB ; Blank screen
- Mov ah, PrSTR
- Mov dx, OFFSET Terminal_message
- Int Dos ; Display message telling user how to get back
- ; to Local BTLink
- term0: cmp inited,0 ; inited yet?
- jz term1 ; no, keep going
-
- test ourarg.flgs,scrsam ; do they want us to leave it alone?
- jnz term1 ; yes, skip redisplay.
-
- call rstscr ; restore screen
-
- term1: mov inited,1 ; remember inited
-
- TRM_Scr:
- call PrtChr_RB
- jmp SHORT term3 ; Have a char...
- nop
-
- jmp SHORT term6 ; No char, go on
-
- term3: and al, 7fh ; Turn off parity for terminal
-
- ; We just got a char from the host, so if we are running under control of a
- ; script we need to let the script processor know what that character is.
-
- cmp Script_processor, 0 ; Is there a script processor to run?
- je PCH_No_script ; No
-
- push ax ; Save reg
- mov ah, 1 ; Code for "character" entry
- call Script_processor ; Let it do its thing
- pop ax ; Restore reg
-
- PCH_No_script:
- mov bx,offset ansbk1 ; Check for Escape Sequence
- call ansbak
- mov bx,offset ansbk2 ; Check for Escape Sequence
- call ansbak
- mov bx,offset ansbk3 ; Check for Escape Sequence
- call ansbak
- mov bx,offset ansbk4 ; Check for Escape Sequence
- call ansbak
- mov bx,offset ansbk5 ; Check for Escape Sequence
- call ansbak
- mov bx,offset ansbk6 ; Check for Escape Sequence
- call ansbak
- Test Ourflgs, MC_Pcon ; Printer Controller on?
- jNZ Term5A ; Yes - print character without displaying it
- term4: push ax
- int fastcon ; go print it
- pop ax
- test ourarg.flgs,capt ; capturing output?
- jz term5 ; no, forget it
- push ax
- call ourarg.captr ; else call the routine
- pop ax
- term5: test ourflgs,fpscr ; print screen toggled on?
- jz term6 ; no, keep going
- Term5A: mov dl,al
- mov ah,lstout ; printer output
- int dos
- term6:
-
- ; Before we are allowed to really check the keyboard, we have to see if
- ; we are running under control of a script. If we are, we have to call
- ; it at its "keyboard" entry instead of reading from the keyboard.
-
- cmp Script_processor, 0 ; Is there a script processor to run?
- je TRM_No_script ; No
-
- TRM_Ck:
- ; mov ah, 1 ; Code to see if anything there
- ; int Kb ; Check input buffer
- ; jz Trm_S1 ; No chars
-
- ; sub ah, ah ; Code zero
- ; int Kb ; Get the char from the buffer
-
- ; cmp al, 3 ; Control-C?
- ; jne TRM_Ck ; No, go see if more chars to be read
-
- ; mov ah, 2 ; Code to shut down
- ; jmp SHORT TRM_S2 ; Join common code
-
- TRM_S1:
- sub ah, ah ; Code for "keyboard" entry
-
- TRM_S2:
- call Script_processor ; Let it do its thing
- test Quit_emulator, 1 ; Is this flag set?
- jnz TRM_S3 ; Yes
-
- jmp TRM_Scr ; No, try for more port characters
-
- TRM_S3: call Close_Screen_RB ; Go set things up right for command mode
- jmp SHORT TRM_Quit ; Go back to other program
-
- TRM_No_script:
- mov di,6 ; get level 1 character
- push es
- int firmwr
- pop es ; don't let firmware steal registers.
- cmp cl,0ffh ; character available?
- je term7 ; Yes - go process it
- cmp cl,1 ; maybe level 2 sequence around
- je TRM_K1 ; Yes, there is
-
- jmp TRM_Scr ; No, forget it
-
- TRM_K1: mov di,2 ; get level 2 character
- push es
- int firmwr
- pop es
- cmp cl,0ffh ; did we really get one?
- je Term8a ; Yes - send char to host,probably some type of
- ; answerback, e.g. cursor position report
-
- jmp TRM_Scr ; No, something strange happening
-
- term7: test ax,fnkey ; function-type key?
- jnz term8 ; yes, can't be escape character, but may
- ; be Quit_emulator (DO) key or
- ; Control-Break key
- cmp al,ourarg.escc ; escape char?
- je TRM_Quit ; yes, exit
- jmp CtlBRK ; No - go check for Control-Break key
- term8: cmp al, 1 ; Is it the DO key?
- je term9 ; Yes - go set flag to exit emulator and exit
- CtlBRK: test ax, ctlkey ; Control-type key?
- jz term8A ; No - can't be Control-Break, go process char
- cmp al, brkkey ; Yes - but is it the Break key?
- jne term8A ; No - go process char
- ; Yes - handle Control-Break as a special case
- ; we have the rainbow transmit the answerback
- ; stored in SETUP mode (This will supersede
- ; the 'SET KEY' feature!!!)
- Mov di, 0
- Mov al, Cntrl_E ; ENQ character
- push es
- Int firmwr ; Send ENQ so Rainbow will transmit its REAL
- pop es ; ANWSERBACK (if user defined one with
- jmp term6 ; SETUP) - and go process it
-
- term8A: call trnout ; perform necessary translations, output char
- jmp TRM_Scr ; and loop around
- term9: or Quit_Emulator, 1 ; Flag that we're exiting terminal emulation
-
- TRM_Quit:
- call savscr ; save terminal session screen
-
- cmp Script_processor, 0 ; Is there a script processor active?
- je TRM_q_no_script ; No
-
- mov ah, 2 ; Code to shutdown
- call Script_processor ; Shut him down
-
- TRM_q_no_script:
- test Quit_Emulator, 1 ; Are we exiting the emulator via the DO key
- jZ term9B ; No - go get 2nd char
-
- Call Restore_command_mode_screen ; Yes - bring back screen
- ret ; and return with exit emulator flag set on
-
- term9B: Mov dx, OFFSET Escape_key_mode_line
- Call PutMod_RB ; Display a mode line for 2nd char posibilities
-
- term9C: Mov di, 4
- Push es
- Int Firmwr ; Look-ahead for a char without removing it
- ; from the input buffer (pretty neat!)
- Pop es
- Cmp cl, 0 ; Saw a char?
- jE term9C ; No - keep looking
-
- Call ClrMod_RB ; Yes - clear mode line and
- Call RstScr ; Restore terminal screen after clearing mode
- ; line
- Ret ; return to process 2nd char (C-Close,
- ; S-Status, B-Break, etc.)
- Term_RB endp
-
-
- ; Set up to run a script processor at selected times, or clear it with zero
-
- Set_up_script_processor_RB PROC
-
- mov Script_Processor, ax ; Set this up, or zero it out
- ret ; That was easy
-
- Set_up_script_processor_RB ENDP
-
-
- ; enter with current terminal character in al, answerback ptr in bx.
- ; calls answerback routine if necessary.
- ; This can be used to make the emulator recognize any sequence.
- ansbak proc near
- push ax ; preserve this
- mov si,[bx].anspt ; get current pointer
- cmp al,[si] ; is it correct?
- jne ansba1 ; no, reset pointers and go on
- inc [bx].anspt ; increment pointer
- dec [bx].ansct ; decrement counter
- jnz ansba2 ; not done, go on
- push bx
- call [bx].ansrtn ; send answerback
- pop bx
- ansba1: mov ax,[bx].ansseq ; get original sequence
- mov [bx].anspt,ax
- mov al,[bx].anslen ; and length
- mov [bx].ansct,al
- ansba2: pop ax
- ret
- ansbak endp
-
- ; Process the receipt of a "Media Copy (Printer Controller On) (MC)" escape
- ; sequence or a "Media Copy (Printer Controller Off) (MC)" escape sequence
-
- Printer_Controller_MC Proc Near
- Xor Ourflgs, MC_Pcon ; Toggle Printer Controller flag
- Ret ; and return
- Printer_Controller_MC Endp
-
- ; enable alternate keypad mode
- enaaky proc near
- mov akeyflg,1 ; remember alternate mode
- mov keyptr,offset altktrn ; set correct translate table
- ret
- enaaky endp
-
- ; disable alternate keypad mode
- deaaky proc near
- mov akeyflg,0
- mov keyptr,offset keytrn
- ret
- deaaky endp
-
- ; enter with char and flags in ax. Does any necessary character translations,
- ; then outputs character
- trnout proc near
- and ax,not cplk ; forget about caps lock key
- test ourarg.flgs,havtt ; any translate table?
- jz trnou2 ; no, just output normally
- mov cx,ourarg.klen
- mov di,ourarg.ktab ; get redefined keys
- repne scasw ; look for this one
- jne trnou2 ; not found, try something else
- sub di,ourarg.ktab
- sub di,2 ; get index
- add di,ourarg.krpl ; get translation address
- mov si,[di] ; this is translation
- mov cl,[si]
- inc si ; pick up length, increment past it
- mov ch,0
- jcxz trnou6 ; no translation, just return
- trnou1: lodsb ; get a char
- push si
- push cx
- call sndhst ; send the character
- pop cx
- pop si
- loop trnou1 ; loop thru rest of translation
- ret ; and return
- trnou2: test ax,fnkey ; function key?
- jz trnou5 ; no, keep going
- and ax,not fnkey ; turn off function bit.
- mov di,offset spckey ; our special keys
- mov cx,spclen ; length of special key table
- repne scasw ; look for it in our table
- jne trnou3 ; not found, maybe arrow key...
- sub di,offset spckey+2 ; get index
- call spchnd[di] ; call appropriate handler
- ret ; and return
- trnou3: mov di,offset arrkey ; look for an arrow-type key...
- mov cx,arrlen ; length of arrow key table
- repne scasb ; is it an arrow key?
- jne trnou4 ; no, forget it
- sub di,offset arrkey+1 ; get index into table
- shl di,1 ; double for word index
- mov si,arrtrn[di] ; get translation
- mov cl,[si]
- inc si
- mov ch,0
- jmp trnou1 ; go send translation
- trnou4: mov di,offset keypad ; look for a keypad key.
- mov cx,keypln
- repne scasb ; is it in keypad?
- jne trnou6 ; no, forget it
- sub di,offset keypad+1
- add di,keyptr ; index into correct translation table
- mov al,[di] ; get translation
- cmp akeyflg,0 ; in alternate keypad mode?
- je trnou5 ; no, just send the char
- push ax ; else save the character
- mov al,esc
- call sndhst
- mov al,'O'
- call sndhst ; send prefix
- pop ax ; get the character back and fall thru...
- trnou5: call sndhst ; send the character
- trnou6: ret
- trnout endp
-
-
- ; handle the print screen key
- prtscr proc near
- push ds ; save data segment
- mov ax,scrseg
- mov ds,ax ; address screen segment
- mov cx,slen ; # of lines on screen
- mov bx,0 ; current line #
- prtsc1: push cx ; save counter
- push bx ; and line ptr
- mov si,ds:[latofs+bx] ; get ptr to line
- mov cx,swidth ; max # of chars/line
- mov di,offset prbuf ; print buffer
- prtsc2: lodsb ; get a byte
- or al,al ; is it a null?
- jne prtsc3 ; no, go on
- mov al,' ' ; yes, replace by space
- prtsc3: stosb ; drop it off
- cmp al,' ' ; is it a space?
- je prtsc4 ; yes, go on
- mov dx,cx ; else remember count at last non-space
- prtsc4: cmp al,0ffH ; end of line?
- loopne prtsc2 ; continue if not end
- mov cx,dx ; count at last non-space, plus 1
- neg cx
- add cx,swidth ; figure out # of chars to print
- mov dx,offset prbuf
- push ds ; save this temporarily
- mov ax,es
- mov ds,ax ; address data segment to print
- jcxz prtsc5 ; 0 length, keep going
- mov bx,4 ; standard printer device
- mov ah,writef2 ; write call
- int dos ; write to the printer
- prtsc5: mov ah,writef2
- mov bx,4
- mov dx,offset crlf
- mov cx,2
- int dos ; follow line with a crlf
- pop ds
- pop bx
- pop cx ; restore counters
- add bx,2 ; point to next line
- loop prtsc1 ; and keep going
- pop ds ; restore registers
- ret ; and return
- prtscr endp
-
- ; toggle print flag...
- togprt proc near
- xor ourflgs,fpscr ; toggle flag
- ret ; and return
- togprt endp
-
- ; Send a character to the host, handle local echo
- sndhst proc near
- push ax ; save the character
- mov ah,al
- call OutChr_RB
- nop
- nop
- nop
- pop ax
- test ourarg.flgs,lclecho ; echoing?
- jz sndhs2 ; no, exit
- int fastcon
- sndhs2: ret ; and return
- sndhst endp
-
-
- ; print a message to the screen. Returns normally.
- tmsg proc near
- mov ah,prstr
- int dos
- ret
- tmsg endp
-
- ; save the screen for later
- savscr proc near
- Mov di, 8
- push es
- Int Firmwr ; Disable cursor
- pop es
- push ds
- mov ax,scrseg
- mov ds,ax
- mov cx,slen ; # of lines to do
- mov bx,0 ; current line #
- mov di,offset ourscr ; place to save screen
- mov dx,offset ourattr ; and to save attributes
- savsc1: push cx ; save current count
- mov si,ds:[latofs+bx] ; get line ptr
- mov cx,swidth ; # of chars/line
- rep movsb ; copy it out
- mov si,ds:[latofs+bx]
- add si,1000H ; this is where attributes start
- xchg dx,di ; this holds attribute ptr
- mov cx,swidth ; # of attrs to move
- rep movsb
- xchg dx,di
- pop cx ; restore counter
- add bx,2 ; increment line ptr
- loop savsc1 ; save all lines and attributes
- pop ds
- call savpos ; might as well save cursor pos
- Mov di, 0Ah
- push es
- Int Firmwr ; Enable cursor
- pop es
- ret
- savscr endp
-
- ; restore the screen saved by savscr
- rstscr proc near
- Mov di, 8
- push es
- Int Firmwr ; Disable cursor
- pop es
- call CmBlnk_RB ; start by clearing screen
- mov si,offset ourscr ; point to saved screen
- mov dx,offset ourattr ; and attributes
- mov cx,slen ; # of lines/screen
- mov bx,101H ; start at top left corner
- rstsc1: push bx
- push cx
- push si ; save ptrs
- push dx
- mov ax,si ; this is source
- call prlina ; print the line
- pop dx
- pop si
- pop cx
- pop bx
- add si,swidth ; point to next line
- add dx,swidth ; and next attributes
- inc bx ; address next line
- loop rstsc1 ; keep restore lines
- call rstpos ; don't forget position
- Mov di, 0Ah
- push es
- Int Firmwr ; Enable cursor
- pop es
- ret
- rstscr endp
-
- ; save the command mode screen for later
- Save_command_mode_screen proc
- Mov di, 8
- push es
- Int Firmwr ; Disable cursor
- pop es
- push ds
- mov ax,scrseg
- mov ds,ax
- mov cx,slen ; # of lines to do
- mov bx,0 ; current line #
- mov di,offset command_mode_screen ; place to save screen
- mov dx,offset command_mode_attrs ; and to save attributes
- savcm1: push cx ; save current count
- mov si,ds:[latofs+bx] ; get line ptr
- mov cx,swidth ; # of chars/line
- rep movsb ; copy it out
- mov si,ds:[latofs+bx]
- add si,1000H ; this is where attributes start
- xchg dx,di ; this holds attribute ptr
- mov cx,swidth ; # of attrs to move
- rep movsb
- xchg dx,di
- pop cx ; restore counter
- add bx,2 ; increment line ptr
- loop savcm1 ; save all lines and attributes
- pop ds
- call Command_savpos ; might as well save cursor pos
- Mov di, 0Ah
- push es
- Int Firmwr ; Enable cursor
- pop es
- And ourflgs, NOT Which_mode ; Flag that we're at terminal
- ; emulation screen now
- ret
- Save_command_mode_screen endp
-
- ; Restore the command mode screen saved by Save_command_mode_screen
- Restore_command_mode_screen proc
- Or ourflgs, Which_mode ; Flag that were are at BTLink
- ; command screen
- Mov di, 8
- push es
- Int Firmwr ; Disable cursor
- pop es
- call CmBlnk_RB ; start by clearing screen
- mov si,offset command_mode_screen ; point to saved screen
- mov dx,offset command_mode_attrs ; and attributes
- mov cx,slen ; # of lines/screen
- mov bx,101H ; start at top left corner
- rstcm1: push bx
- push cx
- push si ; save ptrs
- push dx
- mov ax,si ; this is source
- call prlina ; print the line
- pop dx
- pop si
- pop cx
- pop bx
- add si,swidth ; point to next line
- add dx,swidth ; and next attributes
- inc bx ; address next line
- loop rstcm1 ; keep restore lines
- call Command_rstpos ; don't forget position
- Mov di, 0Ah
- push es
- Int Firmwr ; Enable cursor
- pop es
- ret
- Restore_command_mode_screen endp
-
- ; save cursor position
- savpos proc near
- mov dx,offset curinq ; where is the cursor?
- call tmsg
- mov posbuf,esc ; put an escape in the buffer first
- mov di,offset posbuf+1
- savpo1: mov ah,8 ; read, no echo
- int dos
- cmp al,'R' ; end of report?
- je savpo2 ; yes
- stosb ; no, save it
- jmp savpo1 ; and go on
- savpo2: mov al,'H' ; this ends the sequence when we send it
- stosb
- mov byte ptr [di],'$' ; need this to print it later
- ret ; and return
- savpos endp
-
- ; restore the position saved by savpos
- rstpos proc near
- mov dx,offset posbuf
- call tmsg ; just print this
- ret ; and return
- rstpos endp
-
- ; save command screen cursor position
- Command_savpos proc
- mov dx,offset curinq ; where is the cursor?
- call tmsg
- mov command_posbuf,esc ; put an escape in the buffer first
- mov di,offset command_posbuf+1
- csavpo1:mov ah,8 ; read, no echo
- int dos
- cmp al,'R' ; end of report?
- je csavpo2 ; yes
- stosb ; no, save it
- jmp csavpo1 ; and go on
- csavpo2:mov al,'H' ; this ends the sequence when we send it
- stosb
- mov byte ptr [di],'$' ; need this to print it later
- ret ; and return
- Command_savpos endp
-
- ; restore the position saved by Command_savpos
- Command_rstpos proc
- mov dx,offset command_posbuf
- call tmsg ; just print this
- ret ; and return
- Command_rstpos endp
-
- ; print a 0FFh-terminated line at most swidth long... Pass the line in ax.
- ; cursor position should be in bx.
- ; prlina writes attributes as well, which should be passed in dx.
- prlin proc near
- mov bp,2 ; print characters only
- jmp short prli1
- prlina: xor bp,bp ; 0 means print attributes as well.
- prli1: push es ; this trashes es!!!
- mov si,ax ; better place for ptr
- mov di,ax ; need it here for scan
- mov cx,swidth ; max # of chars in line
- mov al,0ffh ; this marks the end of the line
- repne scasb ; look for the end
- jne prli2 ; not found
- inc cx ; account for pre-decrement
- prli2: neg cx
- add cx,swidth ; figure out length of line
- jcxz prli3 ; 0-length line, skip it.
- mov ax,bp ; writing characters and/or attributes
- mov bp,ds ; wants segment here
- mov di,14H ; fast write to screen
- int firmwr ; pos is in bx, char ptr in si
- prli3: pop es ; restore register
- ret ; and return
- prlin endp
-
-
- ; Jumping to this location is like retskp. It assumes the instruction
- ; after the call is a jmp addr.
-
- RSKP PROC NEAR
- pop bp
- add bp,3
- push bp
- ret
- RSKP ENDP
-
- ; Jumping here is the same as a ret.
-
- R PROC NEAR
- ret
- R ENDP
-
- Do_Server_mode PROC NEAR ; Remote BTLink sent magic escape
- ; sequence to throw us into Server
- ; mode while we were in TERMINAL MODE
- Call Savscr ; Save the current screen
- Call Serrst_RB ; Reset the serial port
- Call Enter_Server ; Jump to Server code
- nop
- nop
- nop
- Call Serini_RB ; Initialize the serial port
- Call Rstscr ; Restore the user's terminal mode
- ; screen
- push dx ; Save a reg
- mov dx, OFFSET Partial_esc_seq ; The string to type
- Call Tmsg ; Type it out so the "J" left over
- ; will be "eaten" by the firmware
- pop dx ; Restore saved register
- Ret
- Do_Server_mode ENDP
-
- Identify PROC
-
- push cx ; Save some registers
- push si
-
- mov cx, Length_of_identification_sequence
- mov si, OFFSET Identification_sequence
-
- Ident_LOP:
- lodsb ; Get the next byte of the sequence
- push cx ; Called routines clobber this reg
- call SndHst ; Send the character to the host
- pop cx ; Get back saved value
- loop Ident_LOP ; Go do another character, if any
-
- pop si ; Restore registers
- pop cx
- ret
-
- Identify ENDP
-
- Close_screen_RB Proc Near ; Called when User quits emulator
- jmp Restore_command_mode_screen ; and enters Command Mode
- Close_screen_RB Endp
-
- code ends
- end
-